home *** CD-ROM | disk | FTP | other *** search
- page ,132 ; print in condensed mode
-
- title STROBE - Monitor a memory field for changes - P. Quale 3/87
- cseg segment para
- assume cs:cseg,ds:cseg,es:nothing,ss:nothing
-
- org 2ch
- env_seg dw ? ;pointer to our copy of environment
- org 80h ;parm list starts here...
- parm_len db ? ;its length
- parm_char db 127 dup(?) ;the parms
- org 100h
- strobe proc near
- begin:
- jmp init ;go to once-only code
-
- prog_id:db 'STROBE 1.02 '
- db 'IBM Internal Use Only '
- db 'P. Quale 03/87'
- id_end equ $
-
- ;history:
- ; 1.01, 05/26/87: revised to incorporate changes suggested by Kevin McCarthy.
- ; The addresses being monitored can now be patched on the fly by patching
- ; new values into the fields intvect and intvect2, which have been
- ; changed from EQU values to doubleword pointers.
-
- ; 1.02, 01/13/89: STROBE now releases its memory when 'R'emoved. Also
- ; removed a potential BRS bug if a derivative program were to have an
- ; ASSUME DS:CSEG directive in the timer interrupt routine, by changing
- ; the exit statement from 'JMP OLDVECT' to 'JMP CS:OLDVECT'.
-
- ;-------macro to simplify window repositioning
- posw macro name,row,column ;convert row/column location
- name equ ((row-1)*160)+((column-1)*2) ;to position in video buffer
- endm
-
- ;-------macro to define field positions within the window
- posf macro name,row,column ;convert line/column location
- name equ corner1+((row-1)*160)+((column-1)*2) ;to pos in video buffer
- endm
-
- db 0 ;waste a byte to align patch area nicely
- old_vect label dword ;original timer vector saved here
- old_ofs dw 0 ;offset
- old_seg dw 0 ;segment
- ; keep old_vect as close to front of program as possible
-
- page
- ;-------entries on this page are grouped together to facilitate
- ;-------changes in window location or storage area(s) being tracked
-
- ;-------next entries define the control block to be "watched"
- ;-------in this case, we watch to see when int 21 gets hooked
- intnum equ 021h ;interrupt number we care about
- intvect dw intnum*4,0 ;offset, segment (patchable)
- prev_value dw 2 dup(?) ;its previous (or initial) contents
-
- ;-------any other memory fields of interest
- intnum2 equ 02fh ;another interrupt number we care about
- intvect2 dw intnum2*4,0 ;offset, segment (patchable)
-
- ;-------next three entries define the window size and location
- posw corner1,1,62 ;upper left corner of window
- posw corner2,1,80 ;upper right corner
- posw corner4,5,80 ;lower right corner
-
- ;-------next entries define location of each field within the window
- posf out1,1,1 ;moving blob goes here on line 1 of window
- posf out2,2,10 ;entry count here at line 2 col 10 of window
- posf out3,3,10 ;contents of major block being tracked
- posf out4,4,10 ;yet another block being tracked
- posf out5,5,10 ;cs:ip of routine running when timer went off
-
- ;-------end of EQUs, etc. peculiar to a specific application of STROBE
- page
-
- ;-------next two equates are needed by the window-clearing code
- windwid equ (corner2-corner1+2)/2 ;width in screen positions
- winddep equ (corner4-corner2+160)/160 ;depth in lines
-
- clknum equ 08h ;timer interrupt number
- clkvect equ clknum*4 ;its vector address
-
- ;-------window attributes/colors used to indicate a value change
- table_mono db 20h,70h,28h,29h ;normal, reversed, bright, underlined
- table_color db 07h,04fh,2fh,5fh ;white on: black, red, green, magenta
- max_change equ 3 ;n'color changes before we recycle (zero-based)
- change_index dw (max_change) ;forces a start at first color
-
- flags db 0 ;flag bits...
- mono equ 01h
- color equ 02h
- sync equ 04h
-
- vidseg dw 0 ;video segment address
- vidsegm equ 0b000h ;video segment address if mono
- vidsegc equ 0b800h ;video segment address if color
- attrib db 0 ;screen attribute byte
- tick_count dw 0 ;cyclic index into tick-display line
- max_tick equ 18 ;limit for tick_count
- blob equ 0feh ;timer-tick char. feh=small square, dbh=big one
- entry_count dw 0 ;count of timer-tick entries to this program
- count_carry db 0 ;how many times entry_count wrapped
- ss_save dw 0 ;ss saved here upon entry
- sp_save dw 0 ;sp saved here
-
- ;-------enter here on timer interrupt
- timer_int:
- assume cs:cseg,ds:nothing,es:nothing,ss:nothing
- pushf ;preserve flags
-
- ;-------switch to our own stack
- cli ;disable interrupts (and keep them that way)
- mov ss_save,ss
- mov sp_save,sp
- push cs
- pop ss
- lea sp,stack_end
- nop
-
- ;-------save the rest of the registers
- push ax
- push bx
- push cx
- push dx
- push bp
- push di
- push si
- push ds
- push es
-
- ;-------set ds for our internal variables, es for video buffer
- push cs
- pop ds
- assume ds:cseg
- push vidseg ;set video segment address
- pop es ;...
-
- ;-------make sure our stack size hasn't been exceeded
- ; (for testing; probably an unnecessary check now)
- mov ax,0fefeh ;string that must still be there
- cmp ax,stack_bottom ;has anyone overrun our stack?
- je check_major ;no
- tight_loop: ;yes, so stop right here and now
- mov ax,05341h ;but leave tracks
- mov es:corner1,ax ;upper left corner of window
- jmp short tight_loop
-
- check_major:
- ;-------check to see if value of memory field we're watching has changed:
- push ds ;save ds for a moment
- assume ds:nothing
- lds bx,dword ptr intvect ;load dword pointer
- mov ax,ds:[bx] ;pick up first 2 bytes of field
- mov bx,ds:[bx+2] ;next 2 bytes
- pop ds
- assume ds:cseg
- cmp ax,prev_value ;still the same?
- jne has_changed ;no
- cmp bx,prev_value+2 ;still the same?
- je clear_window ;yes
- has_changed: ;new value. save new field value and
- call save_major ;alert user by changing window background color
-
- clear_window:
- ;-------clear the screen window and set the background color
- mov al,20h ;get a blank
- mov ah,byte ptr attrib ;pick up window color byte
- mov di,corner1 ;where to start clearing
- mov cx,winddep ;n'lines in window
- call sync_cga ;avoid flicker during writes if CGA display
- clrline:
- push cx ;save line count
- mov cx,windwid ;width of window
- clrbyte:
- mov word ptr es:0[di],ax ;clear one screen position
- inc di
- inc di
- loop clrbyte ;loop for all positions this line
- add di,160-(windwid*2) ;point to next line of window
- pop cx ;all window lines cleared?
- loop clrline ;no
-
- ;-------move blob from left to right on top line to indicate timer-tick rate
- show_blob:
- mov bx,tick_count ;blob's next position on the line
- mov byte ptr es:out1[bx],blob ;get timer-tick character
- inc bx
- inc bx ;compensate for double spacing in video buffer
- cmp bx,max_tick*2 ;have we reached the extreme right?
- jna same_cycle ;not yet
- xor bx,bx ;yes, restart blob at leftmost position
- same_cycle:
- mov tick_count,bx
-
- ;-------for the curious, display count of entries to this routine
- show_count:
- mov ax,entry_count
- inc ax
- jnz no_overflow
- inc byte ptr count_carry
- no_overflow:
- mov entry_count,ax
-
- mov di,out2
- mov ah,byte ptr count_carry
- call cvtbh
- call putchar
- mov ah,byte ptr entry_count+1
- call cvtbh
- call putchar
- mov ah,byte ptr entry_count
- call cvtbh
- call putchar
-
- ;-------get address of routine interrupted when timer went off
- ;-------by pointing into entry-time stack for its cs:ip
- push ss_save
- push sp_save
- pop si
- pop ds
- assume ds:nothing
- add si,2 ;point to saved cs:ip in stack
- mov di,out5 ;where to display it
- call disp_addr
-
- ;-------display the control block of major interest
- show_major:
- mov ax,intvect+2
- mov ds,ax ;set ds to segment to display
- mov si,intvect ;offset to display
- mov di,out3 ;where to display it
- call disp_addr
-
- ;-------display any control blocks of secondary interest here...
- show_minor:
- mov ax,intvect2+2
- mov ds,ax ;set ds to segment to display
- mov si,intvect2 ;offset to display
- mov di,out4 ;where to display it
- call disp_addr
-
- ;-------done. restore the registers
- pop es
- pop ds
- pop si
- pop di
- pop bp
- pop dx
- pop cx
- pop bx
- pop ax
- cli ;no interrupts during upcoming stack-switch
- mov ss,cs:ss_save
- mov sp,cs:sp_save
- popf
- jmp cs:old_vect ;pass control to the routine we unhooked
-
- ;-------subroutines...
-
- ;-------handle a change to the value of the field we're watching:
- ;-------1) save the new value
- ;-------2) switch to the next color
- save_major proc near
- push ax
- push bx
- push ds
- assume ds:nothing
- lds bx,dword ptr intvect ;load dword pointer into ds:bx
- mov ax,ds:[bx] ;first 2 bytes to save
- mov bx,ds:[bx+2] ;next 2 bytes
- pop ds
- assume ds:cseg
- mov prev_value,ax ;save new value
- mov prev_value+2,bx ;...
-
- next_color: ;switch to the next background color
- lea bx,table_mono ;assume mono screen
- test flags,mono ;is it?
- jnz test_max ;yup
- lea bx,table_color
- test_max:
- mov ax,change_index
- inc ax
- cmp ax,max_change ;have we used up all the colors yet?
- jng get_next_attrib ;no
- xor ax,ax ;yes, restart with the first
- get_next_attrib:
- add bx,ax ;point to new attribute char
- mov bl,ds:0[bx] ;pick it up
- mov attrib,bl ;stash it for others to find
- mov change_index,ax ;save index for next time
- pop bx
- pop ax
- ret
- save_major endp
-
- ;-------if using a CGA display, synchronize to avoid flicker
- sync_cga proc near
- test cs:flags,sync ;did user tell us we're on a CGA?
- jz sync_ret ;no, just return to caller
- push ax
- push dx
- mov dx,03dah ;CGA status register
- ;-------the first 4 lines of code below seemed like a good idea,
- ;-------but the CGA flicker goes away without them (on an 8MHz AT),
- ;-------so they're commented out.
- ;ync_loop_1:
- ;;;;;;;;in al,dx ;wait until outside of vertical sync pulse
- ;;;;;;;;test al,08h
- ;;;;;;;;jnz sync_loop_1
- sync_loop_2:
- in al,dx ;now wait for start of new sync pulse
- test al,08h
- jz sync_loop_2
- pop dx
- pop ax
- sync_ret:
- ret
- sync_cga endp
-
- ;-------display an address in seg:offset form
- ; ds:si points to the address to display
- ; es:di is where in the video buffer to put the result
- disp_addr proc near
- mov ah,byte ptr ds:3[si] ;segment
- call cvtbh
- call putchar
- mov ah,byte ptr ds:2[si]
- call cvtbh
- call putchar
-
- mov byte ptr es:[di],':' ;semicolon
-
- add di,2
- mov ah,byte ptr ds:1[si] ;offset
- call cvtbh
- call putchar
-
- mov ah,byte ptr ds:0[si]
- call cvtbh
- call putchar
- ret
- disp_addr endp
-
- ;-------convert the byte in ah to ascii hex and pass result back in ax
- hextabl db '0123456789ABCDEF' ;the hex alphabet
- cvtbh proc near
- push bx ;save
- mov al,ah ;duplicate the argument byte
- shr ah,1 ;shift left nybble over by 4
- shr ah,1 ; ...
- shr ah,1 ; ...
- shr ah,1 ; ...
- and ax,0f0fh ;yields two indices into hex table
- xor bx,bx ;get a zero
- mov bl,ah ;index value for left nybble
- mov ah,cs:hextabl[bx] ;pick up corresponding table char
- mov bl,al ;index for right nybble
- mov al,cs:hextabl[bx] ;pick up table char
- pop bx ;restore
- ret ;return with the answer in ax
- cvtbh endp
-
- ;-------put a pair of ascii hex digits into video buffer
- putchar proc near
- mov es:0[di],ah
- mov es:2[di],al
- add di,4 ;bump index as a convenience to caller
- ret
- putchar endp
-
- stack_bottom dw 0fefeh ;stack underrun sentinel
- stack db 50 dup('STACK ') ;our own stack, probably too big
- resident_paras equ ($-1-cseg)/16 ;padding to bring us to...
- org (resident_paras+1)*16 ;next doubleword boundary
- stack_end equ $ ;end of resident code
-
-
- page
- ;-------begin one-time initialization code...
- init:
- assume cs:cseg,ds:cseg,es:cseg,ss:cseg
-
- ;-------see if any parms given:
- ; M use Monochrome display
- ; C use Color display
- ; S Synchronize to avoid CGA flicker
- ; R Remove (unhook) an active copy of STROBE
-
- mov ah,'R' ;look for 'R'emove
- call parmchk
- jne chk_parm_2 ;not found
- jmp remove
-
- chk_parm_2:
- mov ah,'M' ;look for 'M'ono
- call parmchk
- je setup_mono ;found
-
- mov ah,'S' ;look for 'S'ync
- call parmchk
- jne chk_parm_3 ;not found
- or flags,sync
-
- chk_parm_3:
- mov ah,'C' ;look for 'C'olor
- call parmchk
- je setup_color ;found
-
- ;-------no user screen-choice, so default to the active screen
- int 011h ;ask BIOS what equipment we have
- and al,not 030h ;isolate screen bits
- cmp al,030h ;video mode = mono?
- jne setup_color ;no
-
- setup_mono:
- or flags,mono ;set up for monochrome display
- mov vidseg,vidsegm ;...
- jmp short finish
-
- setup_color:
- or flags,color ;set up for color display
- mov vidseg,vidsegc ;...
-
- finish:
- ;-------release our copy of the environment
- push es ;save es
- mov ax,env_seg ;point es to our copy of the environment
- mov es,ax ;...
- mov ah,49h ;subfunction = free allocated memory
- int 21h ;do it
- pop es ;restore es
-
- call save_major ;save comparand & set up initial window color
-
- ;-------save current interrupt 08 vector; set up to intercept its interrupts.
- ;-------note that although a copy of us may already be resident, we don't care:
- ;-------the copy will get a turn to do its stuff (hopefully in another window)
- xor ax,ax ;get a zero
- mov ds,ax ;point ds to interrupt vectors
- assume ds:nothing
- cli ;no interrupts just now
-
- mov di,ds:clkvect ;pick up offset that's there now
- mov es:old_ofs,di ;stash it
- lea ax,timer_int ;our own interrupt handler offset
- mov ds:clkvect,ax ;replace the old offset
-
- mov ax,ds:clkvect+2 ;pick up segment that's there now
- mov es:old_seg,ax ;stash it
- mov ds:clkvect+2,cs ;replace the old segment address
-
- sti ;enable interrupts again
-
- ;-------terminate and stay resident
- lea dx,stack_end ;get size of resident portion
- shr dx,1 ;convert to paragraphs
- shr dx,1
- shr dx,1
- shr dx,1
- mov ah,31h ;subfunction = tsr
- xor al,al ;exit code = zero
- int 21h ;exit
-
- ;-------remove an active copy of ourself by restoring
- ;-------its saved interrupt vector and freeing its memory
- msg_not_hooked db 'No active copy of STROBE was found',0dh,0ah,'$'
- remove:
- ;-------we can only do this if interrupt 08 vector points to a copy of us
- xor ax,ax
- mov es,ax
- assume es:nothing
-
- mov ax,es:clkvect+2 ;ax = cs of interrupt handler
- mov es,ax ;point es to potential copy of us
- lea si,prog_id ;point to our program id and version
- mov di,si
- mov cx,id_end-prog_id ;number of bytes that must match
- cld ;left-to-right, please
- rep cmpsb ;is it a copy of us?
- jne nocando ;no
- xor ax,ax ;yes, unhook it from interrupt 08 chain
- mov ds,ax
- assume ds:nothing
- cli
- mov ax,es:old_seg ;restore interrupt vector the copy of us saved
- mov ds:clkvect+2,ax
- mov ax,es:old_ofs
- mov ds:clkvect,ax
- sti
- ;-------release memory occupied by copy we just unhooked
- mov ah,49h ;subfunction = free allocated memory
- int 21h ;do it (es still points to the copy)
- jmp short exit_remove ;all done.
- nocando:
- lea dx,msg_not_hooked
- push cs ;be sure we have a good ds
- pop ds ;...
- mov ah,09h ;subfunction = output to display
- int 21h ;display the msg
- exit_remove:
- ret ;exit program
-
- ;-------subroutines...
-
- ;-------search for a user parm matching the character in ah
- parmchk proc near
- xor ch,ch
- mov cl,parm_len ;length of parm list
- jcxz not_found
- mov al,ah ;duplicate the argument
- add al,020h ;lowercase it
- xor bx,bx ;set search index to zero
- next_char:
- cmp al,parm_char[bx]
- je was_found ;match; exit leaving zf = on
- cmp ah,parm_char[bx]
- je was_found ;match; exit leaving zf = on
- inc bx
- loop next_char
- not_found:
- cmp ah,al ;set zf = off
- was_found:
- ret
- parmchk endp
-
- strobe endp
- cseg ends
- end begin